home *** CD-ROM | disk | FTP | other *** search
-
-
-
- DDDDLLLLAAAARRRRRRRRVVVV((((3333SSSS)))) DDDDLLLLAAAARRRRRRRRVVVV((((3333SSSS))))
-
-
-
- NNNNAAAAMMMMEEEE
- DLARRV - compute the eigenvectors of the tridiagonal matrix T = L D L^T
- given L, D and the eigenvalues of L D L^T
-
- SSSSYYYYNNNNOOOOPPPPSSSSIIIISSSS
- SUBROUTINE DLARRV( N, D, L, ISPLIT, M, W, IBLOCK, GERSCH, TOL, Z, LDZ,
- ISUPPZ, WORK, IWORK, INFO )
-
- INTEGER INFO, LDZ, M, N
-
- DOUBLE PRECISION TOL
-
- INTEGER IBLOCK( * ), ISPLIT( * ), ISUPPZ( * ), IWORK( * )
-
- DOUBLE PRECISION D( * ), GERSCH( * ), L( * ), W( * ), WORK( *
- ), Z( LDZ, * )
-
- IIIIMMMMPPPPLLLLEEEEMMMMEEEENNNNTTTTAAAATTTTIIIIOOOONNNN
- These routines are part of the SCSL Scientific Library and can be loaded
- using either the -lscs or the -lscs_mp option. The -lscs_mp option
- directs the linker to use the multi-processor version of the library.
-
- When linking to SCSL with -lscs or -lscs_mp, the default integer size is
- 4 bytes (32 bits). Another version of SCSL is available in which integers
- are 8 bytes (64 bits). This version allows the user access to larger
- memory sizes and helps when porting legacy Cray codes. It can be loaded
- by using the -lscs_i8 option or the -lscs_i8_mp option. A program may use
- only one of the two versions; 4-byte integer and 8-byte integer library
- calls cannot be mixed.
-
- PPPPUUUURRRRPPPPOOOOSSSSEEEE
- DLARRV computes the eigenvectors of the tridiagonal matrix T = L D L^T
- given L, D and the eigenvalues of L D L^T. The input eigenvalues should
- have high relative accuracy with respect to the entries of L and D. The
- desired accuracy of the output can be specified by the input parameter
- TOL.
-
-
- AAAARRRRGGGGUUUUMMMMEEEENNNNTTTTSSSS
- N (input) INTEGER
- The order of the matrix. N >= 0.
-
- D (input/output) DOUBLE PRECISION array, dimension (N)
- On entry, the n diagonal elements of the diagonal matrix D. On
- exit, D may be overwritten.
-
- L (input/output) DOUBLE PRECISION array, dimension (N-1)
- On entry, the (n-1) subdiagonal elements of the unit bidiagonal
- matrix L in elements 1 to N-1 of L. L(N) need not be set. On
- exit, L is overwritten.
-
-
-
-
-
- PPPPaaaaggggeeee 1111
-
-
-
-
-
-
- DDDDLLLLAAAARRRRRRRRVVVV((((3333SSSS)))) DDDDLLLLAAAARRRRRRRRVVVV((((3333SSSS))))
-
-
-
- ISPLIT (input) INTEGER array, dimension (N)
- The splitting points, at which T breaks up into submatrices. The
- first submatrix consists of rows/columns 1 to ISPLIT( 1 ), the
- second of rows/columns ISPLIT( 1 )+1 through ISPLIT( 2 ), etc.
-
- TOL (input) DOUBLE PRECISION
- The absolute error tolerance for the eigenvalues/eigenvectors.
- Errors in the input eigenvalues must be bounded by TOL. The
- eigenvectors output have residual norms bounded by TOL, and the
- dot products between different eigenvectors are bounded by TOL.
- TOL must be at least N*EPS*|T|, where EPS is the machine
- precision and |T| is the 1-norm of the tridiagonal matrix.
-
- M (input) INTEGER
- The total number of eigenvalues found. 0 <= M <= N. If RANGE =
- 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
-
- W (input) DOUBLE PRECISION array, dimension (N)
- The first M elements of W contain the eigenvalues for which
- eigenvectors are to be computed. The eigenvalues should be
- grouped by split-off block and ordered from smallest to largest
- within the block ( The output array W from DLARRE is expected
- here ). Errors in W must be bounded by TOL (see above).
-
- IBLOCK (input) INTEGER array, dimension (N)
- The submatrix indices associated with the corresponding
- eigenvalues in W; IBLOCK(i)=1 if eigenvalue W(i) belongs to the
- first submatrix from the top, =2 if W(i) belongs to the second
- submatrix, etc.
-
- Z (output) DOUBLE PRECISION array, dimension (LDZ, max(1,M) )
- If JOBZ = 'V', then if INFO = 0, the first M columns of Z contain
- the orthonormal eigenvectors of the matrix T corresponding to the
- selected eigenvalues, with the i-th column of Z holding the
- eigenvector associated with W(i). If JOBZ = 'N', then Z is not
- referenced. Note: the user must ensure that at least max(1,M)
- columns are supplied in the array Z; if RANGE = 'V', the exact
- value of M is not known in advance and an upper bound must be
- used.
-
- LDZ (input) INTEGER
- The leading dimension of the array Z. LDZ >= 1, and if JOBZ =
- 'V', LDZ >= max(1,N).
-
- ISUPPZ (output) INTEGER ARRAY, dimension ( 2*max(1,M) )
- The support of the eigenvectors in Z, i.e., the indices
- indicating the nonzero elements in Z. The i-th eigenvector is
- nonzero only in elements ISUPPZ( 2*i-1 ) through ISUPPZ( 2*i ).
-
- GERSCH (workspace) DOUBLE PRECISION array, dimension (2*N)
-
-
-
-
-
- PPPPaaaaggggeeee 2222
-
-
-
-
-
-
- DDDDLLLLAAAARRRRRRRRVVVV((((3333SSSS)))) DDDDLLLLAAAARRRRRRRRVVVV((((3333SSSS))))
-
-
-
- WORK (workspace) DOUBLE PRECISION array, dimension (13*N)
-
- IWORK (workspace) INTEGER array, dimension (6*N)
-
- INFO (output) INTEGER
- = 0: successful exit
- < 0: if INFO = -i, the i-th argument had an illegal value
- > 0: if INFO = 1, internal error in DLARRB if INFO = 2, internal
- error in DSTEIN
-
- FFFFUUUURRRRTTTTHHHHEEEERRRR DDDDEEEETTTTAAAAIIIILLLLSSSS
- Based on contributions by
- Inderjit Dhillon, IBM Almaden, USA
- Osni Marques, LBNL/NERSC, USA
-
-
- SSSSEEEEEEEE AAAALLLLSSSSOOOO
- INTRO_LAPACK(3S), INTRO_SCSL(3S)
-
- This man page is available only online.
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- PPPPaaaaggggeeee 3333
-
-
-
-